Categorical Programming for Data Types with Restricted Parametricity
نویسندگان
چکیده
Many concepts from category theory have proven useful tools for program abstraction, particularly in functional programming. For example, many parametric data types admit operations which are analogous to a functor and a monad. However, some parametric data types whose operations are restricted in their parametricity are not amenable to traditional category-theoretic abstractions in Haskell, despite appearing to have the right structure. This paper explains the limitations of various traditional category-theoretic approaches in Haskell, giving a precise account of the category-theoretic analogy they provide and the implications of restricted parametricity arising from ad-hoc polymorphism provided by type classes in Haskell. Following from this analysis, we generalise Haskell’s notions of functors, monads and comonads, making use of GHC’s new constraint kinds extension, providing techniques for structuring programs with both unrestricted and restricted polymorphism. Many concepts from category theory have been adopted as design patterns for abstraction in programming; we term this approach categorical programming. For example, the notion of a functor is used to abstract map-like operations over parametric data types. In Haskell, “functors” are traditionally defined by a parametric data type together with an instance of the type class Functor : class Functor f where fmap :: (a → b)→ f a → f b The prototypical example is the list data type with the standard map operation: instance Functor [ ] where fmap = map The categorical laws of functors must be checked by hand if functorial behaviour is expected since Haskell has no mechanism for expressing or enforcing such laws. In general, such laws tend to hold only for a strict subset of the language; Functor defines a helpful analogy or model, rather than an actual mathematical functor. Many parametric data types have a map-operation defining a valid Functor instance. However, data types with a map-operation restricted in its parametricity cannot be instances of Functor . For example, the Set data type in Haskell is implemented efficiently using balanced binary-trees thus many of its operations require elements of a set to be orderable such that the internal tree-representation can be balanced [1]. Set has a map-operation of type: Set .map :: (Ord a,Ord b)⇒ (a → b)→ Set a → Set b where the type class constraints (Ord a,Ord b) restrict the parametricity of Set .map to types with orderable values. Since fmap has no constraints on a and b, the type checker rejects a Set-instance of Functor with fmap = Set .map; the signature of fmap describes parametrically polymorphic functions whilst Set .map is ad-hoc polymorphic, with restricted polymorphism and type-dependent behaviour. Many data types similarly have a functorial map-operation that cannot define an instance of Functor because of constraints to the parameter types. The first contribution of this paper makes precise the categorical analogies provided by categorical programming in Haskell using functors and related structures such as monads. Section 1 provides an overview of categorical programming and defines an interpretation for the type structure of programs, in particular for polymorphic and restricted parametricity. The interpretation elucidates the underlying mathematical mismatch between Functor and Set .map: Functor is limited to endofunctors (functors with the same source and target category) whilst Set is a functor mapping from the Ord -subcategory of Haskell. Thus ‘Functor ’ is a misnomer, even as an analogy. A full interpretation of ad-hoc polymorphism in Haskell is not given. Instead we focus on the restricted parametricity provided by ad-hoc polymorphism, ignoring the semantics of type-dependent behaviour by considering just the types of programs. Ad-hoc polymorphism over arbitrary higher-order kinded types is not considered—only the subset of categorical programming with quantification over types of kind ∗. Following the analysis of Functor , the new constraint kinds extension to GHC [4], coupled with Haskell’s type families, is used to define a more general type class of functors not limited to just endofunctors but allowing functors over subcategories, such as Set and other such restricted data types (Section 2). Other commonly used categorical notions in Haskell built upon the concept of functors, such as monads and comonads, similarly do not permit instances for data types with restricted parametric operations. The usual categorical definition of monads and comonads is in terms of endofunctors although monads can be extended to non-endofunctors, called relative monads, as shown by Altenkirch et al. [2, 3]. Section 3 applies the techniques of Section 2, defining classes of relative monads and their dual relative comonads (new in this paper) with examples. The functor and relative monad examples shown here appear elsewhere under the names restricted functors and restricted monads [4, 22]. Our contribution makes precise these constructions from a mathematical perspective. Section 4 concludes with some discussion of generalisations, free theorems that can be deduced for non-endofunctors, and related work. Familiarity with Haskell up to type classes, and the basic concepts of category, functor, and natural transformation, is assumed. Readers unfamiliar with the category theory might first read an introductory text such as Fokkinga’s [7]. 1 Categorical Programming in Haskell We see two distinct approaches to applying category theory in programming: categorical semantics and categorical (or category-oriented) programming. Categorical semantics uses category theory as a metalanguage for defining the semantics of a language, where terms are interpreted in a category that has enough additional structure to satisfy the language properties. For example, Lambek and Scott showed the semantics of well-typed terms in the simply-typed λ-calculus can be interpreted as morphisms in a cartesian-closed category [14]. Categorical programming uses category-theoretic concepts as design patterns and analogies for organising, structuring, and abstracting programs, simplifying both definitions and reasoning. For example, the concept of a monad is used in functional programming to abstract the composition of effect-producing expressions. Whilst categorical semantics provides a categorical interpretation to both the type and term structure of a program, categorical programming instead provides a shallow category-theoretic interpretation of just the type structure, providing a framework for structuring programs using category-theoretic concepts. Most languages do not have a well-defined categorical semantics but still admit some form of categorical programming, albeit with some approximation to the expected axioms. However, a language with a well-defined categorical semantics will likely yield a more precise form of categorical programming, in terms of correctness and reasoning, where the categorical laws of the semantics transfer to the categorical concepts used in programs. For Haskell, Danielsson et al. showed that a subset of monomorphic programs, without general recursion (i.e. without ⊥) and without advanced features such as a type classes, has a categorical semantics in terms of bicartesian-closed categories (bcccs) providing an account of functions, products, and sums [6]. Since non-productive non-termination is usually unintended within a program, the axioms of a bccc may be assumed for the majority of programs in the full Haskell language. Coupled with its applicative syntax and powerful abstraction mechanisms, Haskell is therefore well-suited to categorical programming. However, to be clear, the categorical programming technique frequently deals in analogy rather than actual mathematics. A categorical interpretation for categorical programming in Haskell is now defined, allowing traditional category-theoretic structures used in Haskell to be analysed in Section 1.2 and suitably generalised in Section 2. 1.1 Categorical interpretation for categorical programming Notation: for a category C, its collections of objects and morphisms are C0 and C1. In Haskell types, universal quantification will be explicit, σ and τ range over types, a ranges over type variables (potentially subscripted) and vector notation denotes multiple syntactic elements e.g. a is a group of type variables a0 . . . a|a|. The traditional approach of categorical semantics interprets types as objects of a category and well-typed terms, in a free-variable context, as morphisms from the type of the context to the type of the expression’s result [14]. For categorical programming, we instead provide a more shallow interpretation of the type structure of programs into an imaginary category, Hask, with (monomorphic) Haskell types (of kind ∗) as objects and Haskell functions as morphisms (any non-function expression is taken as a morphism from the unit value/type ()). The interpretation, given by J−K, thus maps types to Hask0 and functions to Hask1 such that Jf :: σ → τK : JσK→ JτK ∈ Hask1 where JσK, JτK ∈ Hask0. Note that Haskell does not provide an actual category Hask (with its functions as morphisms) as the axioms of a category are frequently violated in the presence of general recursion (infinite behaviour). We take Hask to be our analogy for categorical programming purposes, but readers should not think that Haskell readily provides such a category in precise terms. In Hask, every pair of objects (i.e., types) a, b has an object of the type of functions from a to b called the hom-object, denoted Hask(a, b). A category with hom-objects for every pair of objects is called closed. Such categories allow higher-order functions to be interpreted as morphisms from hom-objects. For constant, tuple, and function types, J−K is defined recursively: JcK = c : Hask0 Jσ → τK = Hask(JσK, JτK) : Hask0 iff JσK : Hask0 ∧ JτK : Hask0 J(σ, τ)K = JσK× JτK : Hask0 iff JσK : Hask0 ∧ JτK : Hask0 (1) Parametric Polymorphism Many category-theoretic concepts are defined universally over the objects of a category i.e. “for every object X in C [...].” Since the objects of Hask are Haskell types, parametric polymorphism is central to categorical programming, providing universal quantification over types. Accordingly, only polymorphism over types of kind ∗ will be considered here. The polymorphic λ-calculus can be given a categorical semantics in terms of indexed categories, giving a semantics to type abstraction and application [21]. For our purposes, expanding upon an entire categorical semantics for polymorphism in Haskell is not necessary. Instead, polymorphic types will be interpreted by indexed families. An X-indexed family of Y (written X 7→ Y ) has an Xelement associated to each Y -element in the image. A family f : X 7→ Y will be defined as fx = y, where x is a variable of an X-element and y is a Y -element. The interpretation of polymorphic types is provided at the top-level by J−K∀ and within the binding scope of the universal quantifier by J−KΓ parameterised by a sequence Γ of indices for each free variable of the type it interprets (with some arbitrary canonical order). The definition of J−KΓ is the same as J−K in (1), with Γ passed to recursive sub-terms, with an additional rule for type variables: JaKΓ = a : Hask0 iff a ∈ Γ J∀a . τK∀ = JτK : ( ∏ a Hask)0 7→ Hask0 iff JτKa : Hask0 (2) 1 Indexed families here differ to the notion of type families in GHC/Haskell, which are partial and where the types in the image are potentially unrelated by any common structure; they are not parametric in the sense of Reynolds [20]. where ( ∏ a Hask) is the product category (Hask × . . . × Hask) for the |a|-times product of Hask. The full definition of a product category is irrelevant here since only objects are used. Most importantly, product categories have the property that (C×D)0 ≡ (C0×D0) thus a multi-variable polymorphic type is interpreted as family indexed by a product (tuple) of types. If a = ∅ then ∏ ∅ Hask = 1, where 1 is the unit category with a single object and 10 7→ Hask0 ∼= Hask0. Thus for a type with no type variables the polymorphic interpretation collapses to the monomorphic. As an example, the polymorphic type of the fst function is interpreted: J∀a b . a→ (a, b)Kx,y = Hask(x, (x, y)) : (Hask× Hask)0 7→ Hask0 Polymorphic functions are interpreted as indexed families of morphisms: Jf :: ∀a . σ → τKa = J∀a . σKa → J∀a . τKa : ( ∏ |a| Hask)0 7→ Hask1 (3) Parametric type constructors We consider only parametric types with a single parameter, e.g. data F a = ... defining a type constructor F of kind ∗ → ∗ i.e. F maps a type, of kind ∗, to another type. Parametric polymorphic type constructors will be interpreted similarly to universally quantified types: JF KΓ = F : Hask0 7→ Hask0 iff data F a = . . . Jσ τKΓ = JσKΓ JτKΓ : Hask0 iff JσKΓ : Hask0 7→ Hask0 ∧ JτKΓ : Hask0 (4) We will treat data types as abstract since we are not concerned with the properties of particular data types, only the type constructors. Type classes and ad-hoc polymorphism Rather than give a precise categorical semantics for type classes in general we distinguish two specific uses of type classes relevant to this paper: single parameter type classes parameterised by 1). nullary types of kind ∗ and 2). type constructors of kind ∗ → ∗. Classes parameterised by nullary types are pertinent as they provide type class constraints over Hask objects. Classes parameterised by type constructors are used to abstractly define concepts such as functors, monads, etc. in Haskell. 1). Classes parameterised by nullary types The instances of a type class, class S a (where a has kind ∗), define a subset of Hask objects: the types which have an instance of S . A polymorphic type variable with a type class constraint, e.g., ∀ a . S a ⇒ τ , is therefore restricted in its quantification. Such types will be interpreted as an indexed family S0 7→ Hask0 where S is the subcategory of Hask whose objects are only those with an instance of S and whose morphisms are between types with instances of S . The corresponding subcategory of a type class will be written in sans font. Formally subcategories are defined: Definition 1. For a category C, a subcategory S of C comprises a subclass of the objects of C and a subclass of the morphisms of C such that: – for every morphism f : X → Y ∈ S1 then X,Y ∈ S0; – for every morphism pair f : X → Y, g : Y → Z ∈ S1 then g◦f : X → Z ∈ S1; – for every object X ∈ S0 there is an identity morphism idX : X → X ∈ S1. The parameters of a type class can be constrained, with so-called superclass constraints, implying a partial ordering relation v between the corresponding subcategories, for which Hask is the upper bound. For example, the definition of Ord has a superclass constraint: class Eq a ⇒ Ord a where.... thus any type that is an instance of Ord must be an instance of Eq , i.e., Eq is the superclass of Ord thus Ord v Eq v Hask. Every subcategory S of C has an inclusion functor I : S→ C mapping objects and morphisms into its supercategory. A type with multiple constraints e.g. ∀a . (Sa, Ta)⇒ τ will be interpreted as an (S ∩ T)0 7→ Hask0 family, where S ∩ T is the intersection category which has only the objects and morphisms that are in both S and T. Using subcategories to interpret restricted (ad-hoc) polymorphism, the full interpretation of restricted polymorphic types is provided at the top-level by J−K∀⇒ and within the binding of the universal quantifier and type constraints by J−K∆|Γ where ∆τ is the set of type classes for which there are type class constraints over τ in the interpreted type. The definition of J−K∆|Γ is given in Figure 1 where ( ⋂ S∈∆τ S) is the intersection subcategory S 0 ∩ . . . ∩ S for each class S ∈ ∆τ , i.e., the intersection category of all subcategories corresponding to class constraints on τ . If ∆τ = ∅ i.e. τ is unconstrained, then ⋂ S∈∅ S = Hask. Thus for a type with no constraints, the ad-hoc polymorphic interpretation collapses to the polymorphic interpretation. JaK∆|Γ = a : ( ⋂ S∈∆a S)0 iff a ∈ Γ (5) JcK∆|Γ = c : ( ⋂ S∈∆c S)0 (6) J(σ, τ)K∆|Γ = JσK× JτK : ( ⋂ S∈∆(σ,τ) S)0 iff JσK∆|Γ : C0 ∧ JτK∆|Γ : D0 (7) Jσ → τK∆|Γ = (C u D)(JσK∆|Γ , JτK∆|Γ ) : ( ⋂ S∈∆(σ→τ) S)0 iff JσK∆|Γ : C0 ∧ JτK∆|Γ : D0 (8) Jσ τK∆|Γ = JσK∆|Γ JτK∆|Γ : ( ⋂ S∈∆(σ τ) S)0 iff JσK∆|Γ : Hask0 7→ Hask0 ∧ JτK∆|Γ : C0 (9) Fig. 1. Categorical interpretation of ad-hoc polymorphic types in Haskell. Interpretations of type variables (5), constant types (6), and tuple types (7) resemble the monomorphic and polymorphic interpretations, but now each type is an object of a subcategory corresponding to its constraints. Constraints over type constructors are not interpreted, since we consider only constraints over types of kind ∗, thus the interpretation of type constructors is as before (4). Type constructor application (9) is interpreted as an object of a subcategory, but the type constructor is still a Hask0 7→ Hask0 family. For tuples (7) and constructor applications (9), the subcategories of the subtypes σ and τ do not affect the subcategory of the constructed type since the constructors apply to any objects in Hask thus any objects of any Hask-subcategory. For function types with source and target types in the same subcategory, the hom-object interpretation can be refined from Hask (as in (1)) to the subcategory in which both objects reside. The interpretation of function types (8) generalises further, where a function type with source in C and target in D is a hom-object of C uD, the least upper bound category as defined by v where C u C = C. Note that a hom-object of a subcategory is not necessarily in the subcategory itself. Restricted (ad-hoc) polymorphic functions are interpreted similarly to polymorphic functions (3) as indexed families of morphisms: Jf :: ∀a . S τ ′ ⇒ σ → τK∀⇒ a = J∀a . S τ ′ ⇒ σKa : C0 → J∀a . S τ ′ ⇒ τKa : D0 : ( ∏ a∈a ⋂ S∈∆a S)0 7→ (C u D)1 (10) 2). Type classes parameterised by type constructors Type classes with a single parameter, e.g. class F f , where f :: ∗ → ∗ will be treated, more informally than the other concepts in this section, as meta-mathematical definitions of an abstract F -structure comprising an indexed family f : Hask0 7→ Hask0 together with some indexed families of morphisms (the class methods) related to the parameter indexed family. An instance of the class provides an instance of the structure by providing an indexed family and instances of the operations. 1.2 Interpretation of Functor and restricted map-operations Functor Since Functor is parameterised by a type constructor f of kind ∗ → ∗ it is interpreted as a meta definition, thus class Functor f where fmap :: (a → b)→ f a → f b defines the Functor -structure comprising: – an indexed family f : Hask0 7→ Hask0; – an indexed family of morphisms fmap: JfmapK∀⇒ a,b = Hask(a, b)→ Hask(f a, f b) : (Hask× Hask)0 7→ Hask1 (11) In comparison, a category-theoretic functor F : C → D is defined by: – an object mapping F0 : C0 → D0 mapping all objects A ∈ C0 to F0A ∈ D0; – and a morphism mapping F1 : C1 → D1 mapping all morphisms f : X → Y ∈ C1 to F1 f : F0X → F0 Y ∈ D1 with the usual functorial axioms. An object mapping is equivalent to an objectindexed family of objects, thus in the interpretation of Functor , the class parameter f matches the object mapping in the categorical definition where C = D = Hask. The interpretation of fmap is a morphism in Hask over Hask hom-objects, analogous to the morphism mapping in the categorical definition but embedded within Hask. The embedding of a functor into a category is captured by the notion of enriched, or strong [13], functors [11]. The enriched explanation is not 2 In Haskell, the type of each class method must use the class parameter so that a use of a class method can be statically resolved to a particular class instance. discussed here for space reasons; details can be found in the author’s upcoming thesis. In brief, a strong (equivalently enriched) endofunctor F on a closed (equivalently self-enriched) category C has an object mapping F0 : C0 → C0 and an indexed family of morphisms: Fx,y = C(x, y)→ C(F0 x, F0 y) : (C0 × C0) 7→ C1 corresponding exactly to the interpretation of fmap here, where C = Hask. Thus, Functor models strong endofunctors on Hask. Restricted map-operations The introduction gave the type of the Set .map function which is constrained in the parameter types to the Ord class. The general form of the signature is, for some data type F and class S : F .map :: (S a,S b)⇒ (a → b)→ F a → F b which is interpreted as JF K∀⇒ : Hask0 7→ Hask0 and: JF .mapK∀⇒ a,b = S(a, b)→ Hask(F a, F b) : (S× S)0 7→ Hask1 (12) Thus F .map maps from morphisms of the subcategory S. Although the type constructor F is the family Hask0 7→ Hask0, the interpretation of F .map implies that F is essentially a strong functor F : S → Hask, i.e., not an endofunctor on Hask as captured by Functor . Thus F .map cannot be used to define an F instance of Functor due to the mismatch between (11) and (12). The next section generalises Functor to non-endofunctors using recent features added to GHC/Haskell. The (non-standard) term exofunctor is used for emphasis to describe functors that need not be endofunctors. 2 Generalising Functor from endofunctors to exofunctors A general class of exofunctors for Haskell requires an operation which maps between arbitrary subcategories of Hask in both the source (as in the Set .map) and in the target, i.e. an operation with the following interpretation: JexfmapK∀⇒ a,b = S(a, b)→ T(f a, f b) : (S × S)0 7→ Hask1 (13) A general class of such structures requires parameters for the source and target subcategories associated with the type constructor f . These subcategory parameters will be expressed using type-indexed constraints in Haskell. 2.1 Type-indexed constraints and RFunctor Type classes in Haskell fix the types of their methods with type signatures in the class declaration. The type families extension to GHC allows types of a class method to vary per-instance of a class by defining a family of types associated with the class, indexed by its parameter, and using the family in method signatures [5]. The analogous concept of a constraint family has been previously proposed, allowing the constraints of a class method to vary per-instance by defining a family of constraints associated with a class, indexed by the class parameter [18]. Constraint families provide a solution to the Set-Functor problem. A recent extension to GHC subsumes the constraint family proposal by redefining constraints as types with a distinct constraint kind, thus type families may return types of kind Constraint. The constraint kinds extension, implemented by Bolingbroke [4], negates the need for a syntactic and semantic extension to the type checker to add constraint families. Under the extension, a class constructor, e.g. Ord , is a type constructor of kind ∗ → Constraint . Depending on the context, tuples can be types or constraints i.e. (, ) :: ∗ → ∗ → ∗ or (, ) :: Constraint → Constraint → Constraint (conjunction of constraints) and () :: ∗ or () :: Constraint for the unit type or empty (true) constraint. The Functor class can therefore be generalised using an (associated) type family of constraint-kinded types: class RFunctor f where type SubCats f a :: Constraint type SubCats f a = () rfmap :: (SubCats f a,SubCats f b)⇒ (a → b)→ f a → f b which includes a default empty constraint. Instances for Set and lists are: instance RFunctor Set where type SubCats Set a = Ord a rfmap = Set .map instance RFunctor [ ] where type SubCats [ ] a = () rfmap = map The interpretation of RFunctor depends on the constraints specified by SubCats which vary per-instance of the class and permit constraints over a and b as well as f a and f b, for both the source and target functions. For example: instance RFunctor Foo where type SubCats Foo a = (S a,T (Foo a)) defines subcategories for both the source and target providing an interpretation to rfmap as described by (13). For Set , the interpretation of rfmap is: JrfmapK∀⇒ a,b = Ord(a, b)→ Hask(Set a,Set b) : (Ord× Ord)0 7→ Hask1 (14) Another example exofunctor is the UArray type of unboxed arrays which constrains its elements to primitive types (Int , Float etc.) for which there is an efficient, unboxed storage representation. UArray has a map operation: 3 Constraint kinds are enabled by the pragma {-# LANGUAGE ConstraintKinds #-}. At the time of writing it is also necessary to import GHC .Prim. 4 This definition is the constraint-kinds analogue of the Set-Functor solution shown by Orchard and Schrijvers using constraint families [18]. amap :: (IArray UArray e ′, IArray UArray e, Ix i)⇒ (e ′ → e)→ UArray i e ′ → UArray i e Thus, UArray i (for some index type i) is an exofunctor (IArray UArray)→ Hask with the following instance of RFunctor : instance Ix i ⇒ RFunctor (UArray i) where type SubCats (UArray i) a = IArray UArray a rfmap = amap The category-theoretic structures of monads and comonads are defined over endofunctors together with some operations (natural transformations). The next section generalises monads and comonads to exofunctors. 3 Relative Monads and Comonads Relative Monads Monads in Haskell are traditionally defined by the class: class Monad m where return :: a → m a (>>=) :: m a → (a → m b)→ m b satisfying various laws [26]. The Monad class models a monad in Kleisli triple form defined over an object mapping m : C0 → C0 [15]. An equivalent presentation defines monads in terms of an endofunctor which can be derived from the Kleisli triple form with the following construction of the morphism mapping: instance Monad m ⇒ Functor m where fmap f x = x >>= (return ◦ f ) Since monads are endofunctors, data types that are not endofunctors are not monads. However, data types that are exofunctors may be relative monads, a generalisation of monads for functors J : J→ C where J and C may be distinct [3]. Definition 2. A relative monad over categories J and C comprises: – a functor J : J→ C – an object mapping T : J0 → C0 – a natural transformation (unit) ηX : JX → TX (analogous to return) – a natural transformation (extend) (−)X,Y : (JX → TY ) → (TX → TY ) (analogous to >>= but in prefix form) with the usual monad laws (modulo the presence of J in the types) [2, 3]. Relative monads can be defined in Haskell similarly to exofunctors: class RMonad t where type RSubCats t x :: Constraint unit :: (RSubCats t x )⇒ x → t x extend :: (RSubCats t x ,RSubCats t y)⇒ (x → t y)→ t x → t y As with RFunctor , the exact interpretation of RMonad depends on the constraints specified by RSubCats which define both the subcategories J and C. The indexed family t : Hask0 7→ Hask0 of RMonad corresponds to the object mapping T of relative monads, and is constrained to t : J0 7→ C0 in the types of unit and extend by RSubCats. The two indexed families of morphisms, unit and extend , correspond to the natural transformations in the categorical definition, since natural transformations can be understood as indexed families of morphisms. For RMonad , the J functor of a relative monad is the inclusion functor I : J → C, thus J v C. The inclusion functor I is implicit and elided in the type signatures for RMonad since an inclusion functor between a subcategory and supercategory does not affect the types. The property J v C affects the interpretation of an RMonad instance in two ways depending on the relationship between J and C. Consider an instance of RMonad : instance RMonad Foo where type RSubCats Foo x = (J x ,C (Foo x )) There are two interpretations for unit and extend , depending on J and C: – if J v C therefore J u C = C: unita = a→ Foo a :: J0 7→ C1 extenda,b = C(a,Foo b)→ C(Foo a,Foo b) : (J× J)0 7→ Hask1 – if J 6v C therefore J u C = Hask: unita = a→ Foo a :: J0 7→ Hask1 extenda,b = Hask(a,Foo b)→ C(Foo a,Foo b) : (J× J)0 7→ Hask1 In the first case, the relative monad is over a functor J→ C and in the second over a functor J→ Hask. In terms of programming, this subtlety in the interpretation does not affect the expressivity of the pattern nor introduce added complexity. As an example instance, Set is a relative monad where the object mapping T is given by Set and RSubCats specifies that J = Ord and C = Hask: instance RMonad Set where type RSubCats Set x = Ord x unit x = Set .singleton x extend f x = Set .unions (Prelude.map f (Set .toList x )) Similarly to the definition of a functor from a monad, an exofunctor can be constructed from a relative monad: instance RMonad m ⇒ RFunctor m where type SubCats m a = RSubCats m a rfmap f = extend (unit ◦ f ) Relative comonads Comonads are the dual structure to monads and have been used in functional programming for structuring dataflow programming and streams [24], array computations [17], context-dependent computation [23], and more [12]. However, comonads are less well-known in programming than monads. Comonads can be defined in Haskell via the following type class: class Comonad c where coreturn :: c a → a (= ) :: c a → (c a → b)→ c b with dual laws to those of monads [23, 24], where = is pronounced cobind. Since comonads are less widely-used than monads we provide some intuition and a more involved example. A useful intuition for comonads is of the type c a representing a context-dependent computation, where coreturn evaluates the computation at a default or known “current” context and cobind takes a function c a → b of an operation on a local context and applies it globally, at all contexts. For example, the pointed array comonad comprises an array paired with a particular array index known as the cursor which denotes the current context of execution [17]; coreturn returns the array element pointed to by the cursor, and cobind provides a higher-order convolution-like operation, applying a function to an array at every possible index, calculating a new value for each index: data Arr i a = Arr (Array i a) i instance Ix i ⇒ Comonad (Arr i) where coreturn (Arr arr c) = arr ! c (Arr x c) = f = let es ′ = map (λi → (i , f (Arr x i))) (indices x ) in Arr (array (bounds x ) es ′) c For example, the following defines a discrete Laplace operator which is applied over a one-dimensional array using cobind (where inputData :: [(Int ,Float)]): laplace1D (Arr a i) = if (i > 0 ∧ i < (n − 1)) then a ! (i − 1)− 2 ∗ (a ! i) + a ! (i + 1) else 0.0 n = length inputData x = Arr (array (0,n) inputData) 0 x ′ = x = laplace1D The definition of cobind uses various methods of the IArray class, which provides an interface on array data types, for example: (!) :: (IArray a e, Ix i)⇒ a i e → i → e For the boxed array data type Array used above, there is an instance of IArray which is polymorphic in the element type (instance IArray Array e). Thus Array is an endofunctor Hask→ Hask and is also a monad and a comonad. However, the unboxed array type UArray seen earlier does not have an instance of IArray polymorphic in the element type, but has a limited number of monomorphic instances for primitive types. UArray is thus restricted and is an exofunctor (IArray UArray)→ Hask, therefore cannot be a comonad. However, as with monads, comonads can be generalised to relative comonads on exofunctors. Definition 3. A relative comonad dualises a relative monad, and is defined over categories K and C, comprising: – a functor K : K→ C – an object mapping D : K0 → C0 – a natural transformation (counit): X : DX → KX – a natural transformation (coextend): (−)X,Y : (DX → KY )→ (DX → DY ) with the usual comonad laws (modulo the presence of K in the types). Relative comonads can be defined in Haskell similarly to relative monads: class RComonad d where type RCSubCats d x :: Constraint counit :: RCSubCats d x ⇒ d x → x coextend :: (RCSubCats d x ,RCSubCats d y)⇒ (d x → y)→ d x → d y As with relative monads, the functor K in the categorical definition is taken as the inclusion functor K→ C in RComonad and is implicit in the type signatures as before. The previous analysis for RMonad dualises for RComonad . Unboxed arrays can be defined as a relative comonad thus: data UArr i a = UArr (UArray i a) i instance Ix i ⇒ RComonad (UArr i) where type RCSubCats (UArr i) x = IArray UArray x counit (UArr arr c) = ... -same as coreturn for the Arr comonad coextend f (UArr x c) = ... -same as (= ) for the Arr comonad As another example, the notion of a pointed set common in topology, comprising a set s with a distinguished element x ∈ S, can be defined as a relative comonad on the efficient Set data type: data PSet a = PSet (Set a) a instance RComonad PSet where type RCSubCats PSet x = Ord x counit (PSet s a) = a coextend f (PSet s a) = PSet (Set .map (λa ′ → f (PSet (Set .delete a ′ s) a ′)) s) (f (PSet s a)) where coextend applies its function to every possible combination of a set and a distinguished element, with the distinguished element removed from the set.
منابع مشابه
Parametricity as Isomorphism
We investigatea simple form of parametricity, based on adding \abstract" copies of pre-existing types. Connections are made with the Reynolds-Ma theory of parametricity by logical relations, with the theory of parametricity via dinaturality, and with the categorical notion of equivalence.
متن کاملModels for Polymorphism over Physical Dimensions
We provide a categorical framework for models of a type theory that has special types for physical quantities. The types are indexed by the physical dimensions that they involve. Fibrations are used to organize this index structure in the models of the type theory. We develop some informative models of this type theory: firstly, a model based on group actions, which captures invariance under sc...
متن کاملRelational Parametricity and Separation Logic
Separation logic is a recent extension of Hoare logic for reasoning about programs with references to shared mutable data structures. In this paper, we provide a new interpretation of the logic for a programming language with higher types. Our interpretation is based on Reynolds’s relational parametricity, and it provides a formal connection between separation logic and data abstraction.
متن کاملOn Plotkin-Abadi Logic for Parametric Polymorphism Towards a Categorical Understanding
The idea of parametric polymorphism is that of a single operator that can be used for di erent data types and whose behaviour is somehow uniform for each type. Reynolds [Reynolds, 1983] uses binary relations to de ne a uniformity condition for parametric polymorphism. In [Plotkin & Abadi, 1993] the authors proposed a second order logic for second order lambda-calculus; this logic is able to han...
متن کاملRelational Parametricity for Higher Kinds
Reynolds’ notion of relational parametricity has been extremely influential and well studied for polymorphic programming languages and type theories based on System F. The extension of relational parametricity to higher kinded polymorphism, which allows quantification over type operators as well as types, has not received as much attention. We present a model of relational parametricity for Sys...
متن کاملTowards a Categorical Understanding of Plotkin-Abadi Logic for Parametric Polymorphism
The idea of parametric polymorphism is that of a single operator that can be used for di erent data types and whose behaviour is somehow uniform for each type. This concept was rst proposed by Strachey [13]. Reynolds [9] uses binary relations to de ne a uniformity condition for parametric polymorphism. In [1] Plotkin and Abadi proposed a second order logic for second order lambdacalculus; this ...
متن کاملذخیره در منابع من
با ذخیره ی این منبع در منابع من، دسترسی به آن را برای استفاده های بعدی آسان تر کنید
عنوان ژورنال:
دوره شماره
صفحات -
تاریخ انتشار 2012